home *** CD-ROM | disk | FTP | other *** search
/ Atari Mega Archive 1 / Atari Mega Archive - Volume 1.iso / gnu / smlltalk / smtk_11.zoo / Dictionary.st < prev    next >
Text File  |  1990-05-26  |  10KB  |  373 lines

  1. "======================================================================
  2. |
  3. |   Dictionary Method Definitions
  4. |
  5.  ======================================================================"
  6.  
  7.  
  8. "======================================================================
  9. |
  10. | Copyright (C) 1988, 1989, 1990 Free Software Foundation, Inc.
  11. | Written by Steve Byrne.
  12. |
  13. | This file is part of GNU Smalltalk.
  14. |
  15. | GNU Smalltalk is free software; you can redistribute it and/or modify it
  16. | under the terms of the GNU General Public License as published by the Free
  17. | Software Foundation; either version 1, or (at your option) any later version.
  18. | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT
  19. | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
  20. | FOR A PARTICULAR PURPOSE.  See the GNU General Public License for more
  21. | details.
  22. | You should have received a copy of the GNU General Public License along with
  23. | GNU Smalltalk; see the file COPYING.  If not, write to the Free Software
  24. | Foundation, 675 Mass Ave, Cambridge, MA 02139, USA.  
  25. |
  26.  ======================================================================"
  27.  
  28.  
  29. "
  30. |     Change Log
  31. | ============================================================================
  32. | Author       Date       Change 
  33. | sbyrne      6 May 90      Fixed grow method to preserve associations in use in
  34. |              the dictionary instead of making new ones.  This
  35. |              should be faster, and doesn't break compiled methods
  36. |              that reference global variables when Smalltalk grows.
  37. |
  38. | sbyrne     24 Apr 90      Fix at:ifAbsent: to deal with failure better (and be
  39. |              a tad more efficient).  Kudos (or BarNone's,
  40. |              depending on preference) to Andy Valencia.
  41. |
  42. | sbyrne      7 Apr 90      Modified at:put: to resuse the existing Association
  43. |              if there is one, rather than create a new one all the
  44. |              time.  This was causing lossage when setting global
  45. |              variables in Smalltalk that previous usages weren't
  46. |              being changed.
  47. |
  48. | sbyrne     25 Apr 89      created.
  49. |
  50. "
  51.  
  52. Set variableSubclass: #Dictionary
  53.     instanceVariableNames: ''
  54.     classVariableNames: ''
  55.     poolDictionaries: ''
  56.     category: nil.
  57.  
  58. Dictionary comment: 
  59. 'I implement a dictionary, which is an object that is indexed by
  60. unique objects (typcially instances of Symbol), and associates another
  61. object with that index.  I use the equality operator = to determine
  62. equality of indices.' !
  63.  
  64. "### The initblocks variable should not be globally visible, I think"
  65. "This is a HACK HACK HACK.  We want to reference the InitBlocks global variable
  66. from within some methods in System Dictionary.  However, after this file
  67. redefines at:put: from the built-in one, and until UndefinedObject.st is 
  68. loaded, defining isNil for nil, at:put: for dictionaries does not work
  69. properly.  So we do it here.  The basic problem is that InitBlocks should
  70. maybe be kept elsewhere, and not be globally visible."
  71. Smalltalk at: #InitBlocks put: nil!
  72.  
  73. !Dictionary methodsFor: 'accessing'!
  74. add: anAssociation
  75.     | index |
  76.     index _ self findKeyIndex: anAssociation key.
  77.     (self basicAt: index) isNil
  78.     ifTrue: [ tally _ tally + 1].
  79.     self basicAt: index put: anAssociation.
  80.     ^anAssociation
  81. !
  82.  
  83. at: key put: value
  84.     | index assoc |
  85.     index _ self findKeyIndex: key.
  86.     (assoc _ self basicAt: index) isNil
  87.     ifTrue: [ self basicAt: index
  88.                put: (Association key: key value: value).
  89.           tally _ tally + 1 ]
  90.     ifFalse: [ assoc value: value ].
  91.     ^value
  92. !
  93.  
  94. at: key
  95.     ^self at: key ifAbsent: [ ^self error: 'key not found' ]
  96. !
  97.  
  98. at: key ifAbsent: aBlock
  99.     | assoc |
  100.     assoc _ self basicAt: (self findKeyIndex: key).
  101.     assoc isNil
  102.             ifTrue: [ ^aBlock value ]
  103.             ifFalse: [ ^assoc value ]
  104. !
  105.     
  106. associationAt: key
  107.     ^self associationAt: key ifAbsent: [ ^self error: 'key not found' ]
  108. !
  109.  
  110. associationAt: key ifAbsent: aBlock
  111.     | index assoc|
  112.     index _ self findKeyIndex: key.
  113.     assoc _ self basicAt: index.
  114.     assoc isNil ifTrue: [ ^aBlock value ]
  115.                 ifFalse: [ ^assoc ]
  116. !
  117.  
  118. keyAtValue: value ifAbsent: exceptionBlock
  119.     self associationsDo:
  120.         [ :assoc | value = assoc value
  121.                  ifTrue: [ ^assoc key ] ].
  122.     ^exceptionBlock value
  123. !
  124.  
  125. keyAtValue: value
  126.     ^self keyAtValue: value ifAbsent: []
  127. !
  128.  
  129. keys
  130.     | aSet |
  131.     aSet _ Set new: tally.
  132.     self keysDo: [ :aKey | aSet add: aKey ].
  133.     ^aSet
  134. !
  135.  
  136. values
  137.     | aBag |
  138.     aBag _ Bag new.
  139.     self do: [ :aValue | aBag add: aValue ].
  140.     ^aBag
  141. !!
  142.  
  143.  
  144.  
  145. !Dictionary methodsFor: 'dictionary testing'!
  146.  
  147. includesAssociation: anAssociation
  148.     | assoc |
  149.     assoc _ self associationAt: anAssociation key ifAbsent: [ ^false ].
  150.     ^assoc value = anAssociation value
  151. !
  152.  
  153. includesKey: key
  154.     self associationAt: key ifAbsent: [ ^false ].
  155.     ^true
  156. !
  157.  
  158. includes: anObject
  159.     self do: [ :element | element = anObject ifTrue: [ ^true ] ].
  160.     ^false
  161. !
  162.  
  163. occurrencesOf: aValue
  164.     | count |
  165.     count _ 0.
  166.     self do: [ :element | element = aValue
  167.                     ifTrue: [ count _ count + 1] ].
  168.     ^count
  169. !!
  170.  
  171.  
  172.  
  173. !Dictionary methodsFor: 'dictionary removing'!
  174.  
  175. removeAssociation: anAssociation
  176.     "### does this check the value as well as the key?"
  177.     self removeKey: anAssociation key ifAbsent: [].
  178.     ^anAssociation
  179. !
  180.  
  181. removeKey: key
  182.     ^self removeKey: key ifAbsent: [ ^self error: 'key not found' ]
  183. !
  184.  
  185. removeKey: key ifAbsent: aBlock
  186.     | index assoc |
  187.     index _ self findKeyIndexNoGrow: key ifAbsent: [ ^aBlock value ].
  188.     assoc _ self basicAt: index.
  189.     self basicAt: index put: nil.
  190.     tally _ tally - 1.
  191.     self rehashObjectsAfter: index.
  192.     ^assoc value
  193. !
  194.  
  195. remove: anObject
  196.     self error: 'remove: not allowed in Dictionary'
  197. !
  198.  
  199. remove: anObject ifAbsent: aBlock
  200.     self error: 'remove:ifAbsent: not allowed in Dictionary'
  201. !!
  202.  
  203.  
  204.  
  205. !Dictionary methodsFor: 'dictionary enumerating'!
  206. associationsDo: aBlock
  207.     super do: [ :assoc | aBlock value: assoc ]
  208. !
  209.  
  210. "These could be implemented more efficiently by doing the super do
  211.  directly, or doing the explicit scanning of the dictionary by hand"
  212. keysDo: aBlock
  213.     self associationsDo: [ :assoc | aBlock value: assoc key ]
  214. !
  215.  
  216. do: aBlock
  217.     self associationsDo: [ :assoc | aBlock value: assoc value ]
  218. !
  219.  
  220. collect: aBlock
  221.     | aBag |
  222.     aBag _ Bag new.
  223.     self do: [ :element | aBag add: (aBlock value: element) ].
  224.     ^aBag
  225. !
  226.  
  227. select: aBlock
  228.     | newDict |
  229.     newDict _ self species new.
  230.     self associationsDo:
  231.         [ :assoc | (aBlock value: assoc value)
  232.              ifTrue: [ newDict add: assoc ] ].
  233.     ^newDict
  234. !
  235.  
  236. reject: aBlock
  237.     self shouldNotImplement
  238. !
  239.  
  240. inject: value into: aBlock
  241.     self shouldNotImplement
  242. !!
  243.  
  244.  
  245.  
  246. !Dictionary methodsFor: 'misc math methods'!
  247.  
  248. = aDictionary
  249.     tally ~= aDictionary size ifTrue: [ ^false ].
  250.     self associationsDo:
  251.         [ :assoc | assoc value ~= (aDictionary at: assoc key
  252.                                            ifAbsent: [ ^false ])
  253.                      ifTrue: [ ^false ] ].
  254.     ^true
  255. !
  256.  
  257. hash
  258.     | hashValue |
  259.     hashValue _ tally.
  260.     self associationsDo:
  261.         [ :assoc | hashValue _ hashValue + assoc hash ].
  262.     ^hashValue
  263. !!
  264.  
  265.  
  266.  
  267. !Dictionary methodsFor: 'printing'!
  268.  
  269. printOn: aStream
  270.     aStream nextPutAll: self class name , ' (' .
  271.     self associationsDo:
  272.         [ :assoc | assoc key storeOn: aStream.
  273.                aStream nextPut: $,.
  274.            assoc value storeOn: aStream.
  275.            aStream nextPut: Character space ].
  276.     aStream nextPut: $)
  277. !!
  278.  
  279.  
  280.  
  281. !Dictionary methodsFor: 'storing'!
  282.  
  283. storeOn: aStream
  284.     | hasElements |
  285.     aStream nextPutAll: '(', self class name , ' new'.
  286.     hasElements _ false.
  287.     self associationsDo:
  288.         [ :assoc | aStream nextPutAll: ' at: '.
  289.                    assoc key storeOn: aStream.
  290.                aStream nextPutAll: ' put: '.
  291.            assoc value storeOn: aStream.
  292.            aStream nextPut: $;.
  293.            hasElements _ true ].
  294.     hasElements ifTrue: [ aStream nextPutAll: ' yourself' ].
  295.     aStream nextPut: $)
  296. !!
  297.  
  298.  
  299.  
  300. !Dictionary methodsFor: 'private methods'!
  301.  
  302. rehashObjectsAfter: index
  303.     "Rehashes all the objects in the collection after index to see if any of
  304.     them hash to index.  If so, that object is copied to index, and the
  305.     process repeats with that object's index, until a nil is encountered."
  306.     | i size count assoc |
  307.     i _ index.
  308.     size _ self basicSize.
  309.     c